ReadField Subroutine

public subroutine ReadField(filename, time, dtAggr, dtGrid, aggrType, field, varName, stdName, cellsize, dem, demHiRes, lapse)

read a time varying field from a netcdf file

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename

name of netcdf file

type(DateTime), intent(in) :: time

time of the variable to read

integer, intent(in) :: dtAggr

aggregation time interval

integer, intent(in) :: dtGrid

time interval of grid in netcdf file

character(len=*), intent(in) :: aggrType

aggregation type. 'M' = mean, 'C' = cumulated, 'X' = maximum, 'N' = minimum

type(grid_real), intent(inout) :: field
character(len=*), intent(in), optional :: varName

name of the variable to read

character(len=*), intent(in), optional :: stdName

name of the variable to read

real, intent(in), optional :: cellsize
type(grid_real), intent(in), optional :: dem
type(grid_real), intent(in), optional :: demHiRes
type(grid_real), intent(in), optional :: lapse

Variables

Type Visibility Attributes Name Initial
type(grid_real), public :: gridTemp

temporary grid

type(grid_real), public :: gridTemp3

temporary grid

type(DateTime), public :: gridTime
type(grid_real), public :: gridtemp2

temporary grid

integer, public :: i
integer, public :: j
integer, public :: k
integer, public :: nGrid

number of grid to be read in netcdf file

real, public :: size
character(len=100), public :: standardName
character(len=100), public :: variableName

Source Code

SUBROUTINE ReadField &
!
(filename, time, dtAggr, dtGrid, aggrType, field, varName, &
 stdName, cellsize, dem, demHiRes, lapse )

USE StringManipulation, ONLY : &
! Imported routines:
StringCompact

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT (IN) :: filename !!name of netcdf file
TYPE (DateTime),     INTENT (IN) :: time  !!time of the variable to read
INTEGER,             INTENT (IN) :: dtAggr !!aggregation time interval
INTEGER,             INTENT (IN) :: dtGrid !!time interval of grid in netcdf file
CHARACTER (LEN = *), INTENT (IN) :: aggrType !!aggregation type. 'M' = mean, 'C' = cumulated, 'X' = maximum, 'N' = minimum

CHARACTER (LEN = *), OPTIONAL, INTENT (IN) :: varName !!name of the variable to read
CHARACTER (LEN = *), OPTIONAL, INTENT (IN) :: stdName !!name of the variable to read
REAL,                OPTIONAL, INTENT (IN) :: cellsize
TYPE (grid_real),    OPTIONAL, INTENT (IN) :: dem
TYPE (grid_real),    OPTIONAL, INTENT (IN) :: demHiRes
TYPE (grid_real),    OPTIONAL, INTENT (IN) :: lapse

!Arguments with intent (out):
TYPE (grid_real), INTENT (INOUT) :: field

!Local declarations:
TYPE (grid_real) :: gridTemp !!temporary grid 
TYPE (grid_real) :: gridtemp2 !!temporary grid
TYPE (grid_real) :: gridTemp3 !!temporary grid
INTEGER :: nGrid !! number of grid to be read in netcdf file
TYPE (DateTime) :: gridTime
INTEGER :: i,j,k
CHARACTER (LEN = 100) :: variableName
CHARACTER (LEN = 100) :: standardName
REAL :: size

!------------end of declaration------------------------------------------------

variableName = ''
standardName = ''
IF (PRESENT (cellsize)) THEN
  size  = cellsize
ELSE
  size = 0.
END IF

!read grid in netcdf file
IF (PRESENT(stdName)) THEN
  CALL NewGrid (GridTemp, filename, NET_CDF, stdName=stdName, time = time)
  standardName = stdName
ELSE IF (PRESENT(varName)) THEN
  CALL NewGrid (GridTemp, filename, NET_CDF, variable=varName, time = time)
  variableName = varName
ELSE !read info in field
  IF (TRIM(StringCompact(field % standard_name)) /= '') THEN
    CALL NewGrid (GridTemp, filename, NET_CDF, stdName=field % standard_name, time = time)
    standardName = field % standard_name
  ELSE IF  (TRIM(StringCompact(field % var_name)) /= '') THEN
    CALL NewGrid (GridTemp, filename, NET_CDF, variable=field % var_name, time = time)
    variableName = field % var_name
  ELSE
    CALL Catch ('error', 'MeteoUtilities',   &
			    'missing standard or variable name in grid while calling ReadField' )
  END IF
END IF

!compute number of grid to be read in netcdf file
nGrid = INT (dtAggr / dtGrid)

gridTime = time
!read other grids in netcdf file
DO k = 1, nGrid - 1 
  gridTime = gridTime + dtGrid
   
  IF (PRESENT(stdName)) THEN
      CALL NewGrid (gridTemp3, filename, NET_CDF, stdName=stdName, time = gridTime)
  ELSE IF (PRESENT(varName)) THEN
      CALL NewGrid (gridTemp3, filename, NET_CDF, variable=varName, time = gridTime)
  ELSE !read info in field
      IF (TRIM(StringCompact(field % standard_name)) /= '') THEN
        CALL NewGrid (gridTemp3, filename, NET_CDF, stdName=field % standard_name, time = gridTime)
      ELSE IF  (TRIM(StringCompact(field % var_name)) /= '') THEN
        CALL NewGrid (gridTemp3, filename, NET_CDF, variable=field % var_name, time = gridTime)
      ELSE
        CALL Catch ('error', 'MeteoUtilities',   &
			        'missing standard or variable name in grid while calling ReadField' )
      END IF
  END IF
  
  DO i = 1, gridTemp % idim
    DO j = 1, gridTemp % jdim
      IF (gridTemp % mat (i,j) /= gridTemp % nodata ) THEN
         SELECT CASE (aggrType)  
           CASE ('M','C') !mean or cumulated
              gridTemp % mat(i,j) = gridTemp % mat(i,j) + gridTemp3 % mat(i,j)
           CASE ('N') !minimum
              gridTemp % mat (i,j) = MIN (gridTemp % mat (i,j), gridTemp3 % mat(i,j))
           CASE ('X') !maximum
              gridTemp % mat (i,j) = MAX (gridTemp % mat (i,j), gridTemp3 % mat(i,j))
         END SELECT
      END IF
    END DO
  END DO
  CALL GridDestroy (gridTemp3) 
END DO

SELECT CASE (aggrType)
  CASE ('M') !mean
    DO i = 1, gridTemp % idim
      DO j = 1, gridTemp % jdim
        IF (gridTemp % mat (i,j) /= gridTemp % nodata ) THEN
          gridTemp % mat (i,j) = gridTemp % mat (i,j) / REAL (nGrid)
        END IF
      END DO
    END DO
END SELECT

!update attribute
  field % next_time = gridTemp % next_time
  field % reference_time = gridTemp % reference_time
  field % current_time = gridTemp % current_time 
  field % time_index = gridTemp % time_index
  field % time_unit = gridTemp % time_unit
  field % var_name = gridTemp % var_name
  field % standard_name = gridTemp % standard_name
  field % file_name = gridTemp % file_name
  
!coordinate conversion
IF ( .NOT. gridTemp % grid_mapping == field % grid_mapping) THEN
  !set Coordinate reference system of temporary grid
  gridTemp2 % grid_mapping = field % grid_mapping
  !convert coordinate
  IF (size > 0.) THEN
      CALL GridConvert (gridTemp, gridTemp2, cellsize = size)
  ELSE
       CALL GridConvert (gridTemp, gridTemp2)
  END IF

  !apply lapse rate 
  IF (PRESENT (dem) .AND. PRESENT (demHiRes) .AND. PRESENT (lapse) ) THEN
    DO i = 1, gridTemp2 % idim
     DO j = 1, gridTemp2 % jdim
        IF (gridTemp2 % mat(i,j) /= gridTemp2 % nodata) THEN
              gridTemp2 % mat (i,j) = gridTemp2 % mat (i,j) + &
                      ( demHiRes % mat(i,j) - dem % mat (i,j) ) * &
                      lapse % mat(i,j) 
              
        END IF
     END DO
    END DO
  END IF


  !resample grid
  CALL GridResample (gridTemp2, field)
  CALL GridDestroy (gridTemp)
  CALL GridDestroy (gridTemp2)
ELSE
  !resample grid
  CALL GridResample (gridTemp, field)
  CALL GridDestroy (gridTemp) 
END IF

RETURN


END SUBROUTINE ReadField